home
***
CD-ROM
|
disk
|
FTP
|
other
***
search
/
Magnum One
/
Magnum One (Mid-American Digital) (Disc Manufacturing).iso
/
d20
/
msgq160s.arc
/
EXECSWAP.ASM
< prev
next >
Wrap
Assembly Source File
|
1991-10-26
|
21KB
|
844 lines
;
; EXECSWAP.ASM
; Swap memory and exec another program
; Copyright (C) 1988 TurboPower Software
; May be used freely as long as due credit is given
; Modified by P.J. Muller from code in Dr. Dobbs
;
; Modifications:
; o Save DS on Stack instead of reloading with SEG Data.
; o Rewrote most of the remaining Pascal into Assembler
; o Moved variables from Data segment to Code segment
; o Use Get PSP Dos Function instead of PrefixSeg variable
; o Removed Data segment totally
; o Flush the swap file before Exec (but it still says open)
; o Now creates unique filename and use SwapFileName as path prefix
;
; Note: If a path is specified for SwapFileName, it must be a full path
; including a drive specifier and trailing backslash. Otherwise, an
; empty string must be passed and the current drive and directory will be
; used.
;
; The code is now very language INdependant
;
; Reference: Dr. Dobbs Journal, April 1989
;
; Compile for Turbo Pascal: TASM /dTP=1 EXECSWAP
; Compile for Turbo C: TASM EXECSWAP
;
IF TP
Code SEGMENT WORD PUBLIC
ELSE
Code SEGMENT WORD PUBLIC 'CODE'
ENDIF
ASSUME CS:Code, DS:NOTHING, ES:NOTHING, SS:NOTHING
PUBLIC ExecWithSwap, ShutdownExecSwap, InitExecSwap
PUBLIC BytesSwapped, EmsAllocated, FileAllocated
FileAttr EQU 6 ; Swap file attr (hidden+system)
EmsPageSize EQU 16384 ; EMS page size
FileBlockSize EQU 32768 ; Swap file block size
StkSize EQU 128 ; Temp stack size
lo EQU (WORD PTR 0) ; Convenient typecasts
hi EQU (WORD PTR 2)
ofst EQU (WORD PTR 0)
segm EQU (WORD PTR 2)
; Variables in CS
EmsDevice DB 'EMMXXXX0',0 ; Name of EMS device driver
UsedEms DB 0 ; 1 if swapping to EMS, 0 if to file
BytesSwappedCS DD 0 ; Bytes to move during a swap
FileAllocatedF DB 0 ; Was a file allocated?
EmsAllocatedF DB 0 ; Was EMS allocated?
EmsHandle DW 0 ; EMS handle
FrameSeg DW 0 ; Segment of EMS page window
FIleHandle DW 0 ; DOS file handle
PrefixSegCS DW 0 ; Segment of base of program
Status DW 0 ; ExecSwap status code
LeftToSwap DD 0 ; Bytes left to move
SaveSP DW 0 ; Original SP
SaveSS DW 0 ; Original SS
PathPtr DD 0 ; Pointer to program to execute
CmdPtr DD 0 ; Pointer to command line to execute
ParasWeHave DW 0 ; Paragraphs allocated to process
CmdLine DB 128 DUP(0) ; Terminated command line passed to DOS
Path DB 64 DUP(0) ; Terminated path name passed to DOS
FileBlock1 DB 16 DUP(0) ; FCB passed to DOS
FileBlock2 DB 16 DUP(0) ; FCB passed to DOS
EnvironSeg DW 0 ; Segment of environment for child
CmdLinePtr DD 0 ; Pointer to terminated command line
FilePtr1 DD 0 ; Pointers to FCBs
FilePtr2 DD 0
TempStack DB StkSize DUP(0) ; Temp stack
StackTop LABEL WORD ; Initial TOS
; Macros
MovSeg MACRO Dest, Src ; MOV seg,seg
push Src
pop Dest
ENDM
MovMem MACRO Dest, Src ; MOV AX,mem; MOV mem,AX
mov ax,Src
mov Dest,ax
ENDM
InitSwapCount MACRO ; Init counter for bytes to swap
MovMem LeftToSwap.lo, BytesSwappedCS.lo
MovMem LeftToSwap.hi, BytesSwappedCS.hi
ENDM
SetSwapCount MACRO BlkSize ; Return CX=bytes to move this block
LOCAL FullBlk ; and reduce total bytes left to move
mov cx,BlkSize ; Assume we'll write a full block
cmp LeftToSwap.hi,0 ; Is high word still non-zero?
jnz FullBlk ; Jump if so
cmp LeftToSwap.lo,BlkSize ; Low word still a block or more?
jae FullBlk ; Jump if so
mov cx,LeftToSwap.lo ; Otherwise, move what's left
FullBlk:sub LeftToSwap.lo,cx ; Reduce number left to move
sbb LeftToSwap.hi,0
ENDM
NextBlock MACRO SegReg, BlkSize ; Point SegReg to next block to move
mov ax,SegReg
add ax,BlkSize/16 ; Add paragraphs to next segment
mov segreg,ax ; next block to move
mov ax,LeftToSwap.lo
or ax,LeftToSwap.hi ; Bytes left to move?
ENDM
EmsCall MACRO FuncAH ; Call EMM and prepare to check result
mov ah,FuncAH
int 67h
or ah,ah ; Error code in AH
ENDM
DosCallAH MACRO FuncAH ; Call DOS subfunction AH
mov ah,FuncAH
int 21h
ENDM
DosCallAX MACRO FuncAX ; Call DOS subfunction AX
mov ax,FuncAX
int 21h
ENDM
InitSwapFile MACRO
mov bx,FileHandle ; BX=handle of swap file
xor cx,cx
xor dx,dx ; Start of file
DosCallAX 4200h ; Dos File Seek
ENDM
HaltWithError MACRO Level ; Halt if non-recoverable error occurs
mov al,Level ; Set errorlevel
DosCallAX 4Ch
ENDM
MoveFast MACRO ; Move CX bytes from DS:SI to ES:DI
cld ; Forward
shr cx,1 ; Convert to words
rep movsw ; Move the words
rcl cx,1 ; Get the odd byte, if any
rep movsb ; Move it
ENDM
SetTempStack MACRO ; Switch to Temp stack
mov ax,OFFSET StackTop ; Point to TOS
mov bx,cs ; Temp stack in this code segment
cli
mov ss,bx
mov sp,ax
sti
ENDM
; FUNCTION ExecWithSwap(Path, CmdLine :String) :Word;
; Saves BP and DS
ExecWithSwap PROC FAR
push bp
mov bp,sp ; set up stack frame
push ds ; Save DS
; Move variables to CS where we can easily access them later
mov Status,1 ; Assume failure
les di,[bp+6] ; ES:DI -> CmdLine
mov CmdPtr.ofst,DI
mov CmdPtr.segm,ES ; CmdPtr -> command line string
les di,[bp+10] ; ES:DI -> Path
mov PathPtr.ofst,DI
mov PathPtr.segm,ES ; PathPtr -> path to execute
mov SaveSP,sp ; Save stack position
mov SaveSS,ss
mov ah,81 ; Get our PSP (undocumented)
int 21h
mov PrefixSegCS,bx ; Save it
InitSwapCount ; Init bytes LeftToSwap
; Check for swapping to EMS or file
cmp EmsAllocatedF,0 ; Check flag for EMS method
jz NotEms ; Jump if EMS not used
jmp short WriteE ; Swap to EMS
NotEms: cmp FileAllocatedF,0 ; Check flag for swap file method
jnz WriteF ; Swap to file
jmp ESDone ; Exit if no swapping method set
; Write to swap file
WriteF: MovSeg DS,CS ; DS = CS
InitSwapFile ; Seek to start of swap file
jnc EF0 ; Jump if success
jmp ESDone ; Exit if error
EF0: SetSwapCount FileBlockSize ; CX = bytes to write
mov dx,OFFSET FirstToSave ; DS:DX -> start of region to save
DosCallAH 40h ; File Write
jc EF1 ; Jump if write error
cmp ax,cx ; All bytes written?
jz EF2 ; Jump if so
EF1: jmp ESDone ; Exit if error
EF2: NextBlock DS,FileBlockSize ; Point DS to next block to write
jnz EF0 ; Loop if bytes left to write
; Flush the swap file
DosCallAH 45h ; Dup file handle BX
jc EF20 ; ignore close if error
mov bx,ax ; BX = dup handle
DosCallAH 3Eh ; Close dup handle
EF20: mov UsedEms,0 ; Flag we used swap file for swapping
jmp short SwapDone ; Done swapping out
; Write to EMS
WriteE: mov es,FrameSeg ; ES -> page window
mov dx,EmsHandle ; DX = handle of our EMS block
xor bx,bx ; BX = initial logical page
MovSeg ds,cs ; DS = CS
EE0: xor al,al ; Physical page 0
EmsCall 44h ; Map physical page
jz EE1 ; Jump if success
jmp ESDone ; Exit if error
EE1: SetSwapCount EmsPageSize ; CX = bytes to move
xor di,di ; ES:DI -> base of EMS page
mov si,OFFSET FirstToSave ; DS:SI -> region to save
MoveFast ; Move CX bytes from DS:SI to ES:DI
inc bx ; Next logical page
NextBlock ds,EmsPageSize ; Point ds to next page to move
jnz EE0 ; Loop if bytes left to move
mov UsedEms,1 ; Flag we used EMS for swapping
; Shrink memory allocated to this process
SwapDone:mov ax,PrefixSegCS
mov es,ax ; ES = segment of our memory block
dec ax
mov ds,ax ; DS = segment of memory control block
mov cx,ds:[0003h] ; CX = current paragraphs owned
mov ParasWeHave,cx ; Save current paragraphs owned
SetTempStack ; Switch to temporary stack
mov ax,OFFSET FirstToSave+15
mov cl,4
shr ax,cl ; Convert offset to paragraphs
add bx,ax
sub bx,PrefixSegCS ; BX = new paragraphs to keep
DosCallAH 4Ah ; SetBlock
jnc EX0 ; Jump if successful
jmp EX5 ; Swap back and exit
; Set up parameters and call DOS exec
EX0: mov ax,es:[002ch] ; Get environement segment
mov EnvironSeg,ax
MovSeg es,cs ; ES = CS
lds si,PathPtr ; DS:SI -> path to execute
mov di,OFFSET Path ; ES:DI -> local ASCIIZ copy
cld
lodsb ; Read current length
cmp al,63 ; Truncate if exceeds space set aside
jb EX1
mov al,63
EX1: mov cl,al
xor ch,ch ; CX = bytes to copy
rep movsb
xor al,al
stosb ; ASCIIZ terminate
lds si,CmdPtr ; DS:SI -> Command line to pass
mov di,OFFSET CmdLine ; ES:DI -> Local Terminated copy
lodsb ; Read current length
cmp al,126 ; Truncate if exceeds space set aside
jb EX2
mov al,126
EX2: stosb
mov cl,al
xor ch,ch ; CX = bytes to copy
rep movsb
mov al,0Dh
stosb ; Terminate with ^M
MovSeg ds,cs ; DS = CS
mov si,OFFSET CmdLine
mov CmdLinePtr.ofst, si
mov CmdLinePtr.segm, ds ; Store pointer to command line
inc si
mov di,OFFSET FileBlock1
mov FilePtr1.ofst, di
mov FilePtr1.segm, es ; Store pointer to filename 1, if any
DosCallAX 2901h ; Parse FCB
mov di,OFFSET FileBlock2
mov FilePtr2.ofst, di
mov FilePtr2.segm, es ; Store pointer to filename 2, if any
DosCallAX 2901h ; Parse FCB
mov dx,OFFSET Path
mov bx,OFFSET EnvironSeg
DosCallAX 4B00h ; Exec
jc EX3 ; Jump if error in DOS call
xor ax,ax ; return zero for success
EX3: mov Status,ax ; save Dos error code
; Set up temporary stack and reallocate original memory block
SetTempStack
mov es,PrefixSegCS
mov bx,ParasWeHave
DosCallAH 4Ah ; SetBlock
jnc EX4 ; Jump if no error
HaltWithError 0FFh ; Must halt if failure here
EX4: InitSwapCount ; Init LeftToSwap
; Check which swap method is in use
EX5: cmp UsedEms,0
jz ReadF ; Jump to read back from file
jmp short ReadE ; Read back from EMS
; Read back from swap file
ReadF: MovSeg ds,cs ; DS = CS
InitSwapFile ; Seek to start of swap file
jnc EF3 ; Jump if we succeeded
HaltWithError 0FEh ; Must halt if failure here
EF3: SetSwapCount FileBlockSize ; CX = bytes to read
mov dx,OFFSET FirstToSave ; DS:DX -> start of region to restore
DosCallAH 3Fh ; Read file
jnc EF4 ; Jump if no error
HaltWithError 0FEh ; Must halt if failure here
EF4: cmp ax,cx
jz EF5 ; Jump if full block read
HaltWithError 0FEh ; Must halt if failure here
EF5: NextBlock ds,FileBlockSize ; Point DS to next page to read
jnz EF3 ; Jump if bytes left to read
jmp short ESDone ; We're done
; Copy back from EMS
ReadE: mov ds,FrameSeg ; DS -> page window
mov dx,EmsHandle ; DX = handle of our EMS block
xor bx,bx ; BX = initial logical page
MovSeg es,cs ; ES = CS
EE3: xor al,al ; Physical page 0
EmsCall 44h ; Map physical page
jz EE4 ; Jump if success
HaltWithError 0FDh ; Must halt if failure here
EE4: SetSwapCount EmsPageSize ; CX = Bytes to move
xor si,si ; DS:SI -> base of EMS page
mov di,OFFSET FirstToSave ; ES:DI -> region to restore
MoveFast ; Move CX bytes from DS:SI to ES:DI
inc bx ; Next logical page
NextBlock es, EmsPageSize ; Point ES to next page to move
jnz EE3 ; Jump if so
ESDone: cli ; Switch back to original stack
mov ss,SaveSS
mov sp,SaveSP
sti
pop ds ; Restore DS
mov ax,Status ; Return status
pop bp
ret 8 ; Remove parameters and return
ExecWithSwap ENDP
;-------------------------------------------------------------------------
; Label EVEN marks first location to swap
FirstToSave:
; Local CS data which can be swapped out (PJM)
SwapName DB 80 DUP(0) ; ASCIIZ swap file name
; FUNCTION AllocateSwapFile :Boolean;
AllocateSwapFile PROC NEAR
mov cx,FileAttr ; Attribute for swap file
push ds
MovSeg ds,cs
mov dx,OFFSET SwapName ; DS:DX -> ASCIIZ swap name
DosCallAH 3Ch ; Create file
pop ds
mov FileHandle,ax ; Save handle assuming success
mov al,0 ; Assume failure
jc ASDone ; Failed if carry set
inc al ; Return true for success
ASDone: ret
AllocateSwapFile ENDP
; PROCEDURE DeallocateSwapFile;
DeallocateSwapFile PROC NEAR
push ds
mov bx,FileHandle ; Handle of swap file
DosCallAH 3Eh ; Close file
xor cx,cx ; normal Attribute
MovSeg ds,cs
mov dx,OFFSET SwapName ; DS:DX -> ASCIIZ swap name
DosCallAX 4301h ; Set file attribute
DosCallAH 41h ; Delete file
pop ds
ret
DeallocateSwapFile ENDP
; FUNCTION EmsInstalled :Boolean;
EmsInstalled PROC NEAR
push ds
MovSeg ds,cs ; DS = CS
mov dx,OFFSET EmsDevice ; DS:DX -> EMS driver name
DosCallAX 3D02h ; Open for read/write
pop ds
mov bx,ax ; Save handle in case one returned
mov al,0 ; Assume False
jc EIDone
DosCallAH 3Eh ; Close file
mov al,1 ; Return True
EIDone: ret
EmsInstalled ENDP
; FUNCTION EmsPageFrame :Word;
EmsPageFrame PROC NEAR
EmsCall 41h ; Get Page frame
mov ax,bx ; AX = segment
jz EPDone ; Done if Error = 0
xor ax,ax ; else segment = 0
EPDone: ret
EmsPageFrame ENDP
; FUNCTION AllocateEmsPages(NumPages :Word) :Word;
AllocateEmsPages PROC NEAR
mov bx,sp ; Set up stack frame
mov bx,ss:[bx+2] ; BX = NumPages
EmsCall 43h ; Allocate EMS
mov ax,dx ; Assume success
jz APDone ; Done if not 0
mov ax,0FFFFh ; $FFFF for failure
APDone: ret 2 ; Remove parameter and return
AllocateEmsPages ENDP
; PROCEDURE DeallocateEmsHandle(Handle :Word);
DeallocateEmsHandle PROC NEAR
mov bx,sp ; Set up stack frame
mov dx,ss:[bx+2] ; DX = Handle
EmsCall 45h ; Deallocate EMS
ret 2 ; Remove parameter and return
DeallocateEmsHandle ENDP
; FUNCTION DefaultDrive :Char;
DefaultDrive PROC NEAR
DosCallAH 19h ; Get default drive
add al,'A' ; Convert to character
ret
DefaultDrive ENDP
; FUNCTION DiskFree(Drive :Byte) :LongInt;
DiskFree PROC NEAR
mov bx,sp ; Set up stack frame
mov dl,ss:[bx+2] ; DL = Drive to check
DosCallAH 36h ; Get disk space
mov dx,ax ; Return 0FFFFFFFFh for failure
cmp ax,0FFFFh ; Bad drive number?
jz DFDone ; Jump if so
mul cx ; AX = bytes/cluster
mul bx ; DX:AX = bytes free
DFDone: ret 2 ; Remove parameter and return
DiskFree ENDP
;
; The code that follows was added by PJM
;
; PROCEDURE ShutdownExecSwap;
ShutdownExecSwap PROC FAR
cmp EmsAllocatedF, 0 ; Was EMS allocated?
je SE1 ; no, check file
; Deallocate EMS
push EmsHandle ; Parameter
call DeallocateEmsHandle
mov EmsAllocatedF, 0
jmp short SEDone
SE1: cmp FileAllocatedF,0 ; Was a file allocated?
je SEDone ; no, exit
; Deallocate File
call DeallocateSwapFile
mov FileAllocatedF,0
SEDone: ret
ShutdownExecSwap ENDP
; FUNCTION Normalize(P :Pointer) :Pointer;
;
; 04d P
; 02d RetAddr (2)
; BP -> BP
Normalize PROC NEAR
push bp
mov bp,sp
mov ax,[bp+6]
xor dx,dx ; DX:AX = Seg(P^)
REPT 4
shl ax,1
rcl dx,1 ; DX:AX = DX:AX shl 4
ENDM
add ax,[bp+4]
adc dx,0 ; DX:AX = DX:AX + Ofs(P^)
pop bp
ret 4
Normalize ENDP
; FUNCTION CanOpen(Name :ASCIIZ) :Boolean;
CanOpen PROC NEAR
mov bx,sp ; Stack frame
push ds
lds dx,ss:[bx+2]
DosCallAX 3D00h ; Open file for reading
jc CO1
mov bx,ax ; handle
DosCallAH 3Eh ; Close file
mov al,1 ; Can open file
jmp short CO2
CO1: xor al,al ; Can't open file
CO2: pop ds
ret 4
CanOpen ENDP
; FUNCTION HexPrint(Dest :Pointer; Val :Word) :Pointer;
;
; 04d Dest (4)
; 02d Val (2)
HexPrint PROC NEAR
mov bx,sp ; Stack frame
les di,ss:[bx+4]
cld
mov al,ss:[bx+3]
mov cl,4
shr al,cl
call Digit
mov al,ss:[bx+3]
and al,15
call Digit
mov al,ss:[bx+2]
mov cl,4
shr al,cl
call Digit
mov al,ss:[bx+2]
and al,15
call Digit
mov ax,di
mov dx,es
ret 6
Digit: add al,'0'
cmp al,'9'
jbe D0
add al,'A'-'9'-1
D0: stosb
ret
HexPrint ENDP
; FUNCTION GetDirectory(Buf :Pointer) :Pointer
GetDirectory PROC NEAR
mov bx,sp
push ds
lds si,ss:[bx+2]
mov byte ptr [si],0
xor dl,dl
DosCallAH 47h ; Get default directory
MovSeg es,ds
mov di,si ; ES:DI = DS:SI
cld
mov cx,-1
xor al,al
repnz scasb
dec di
not cx
dec cx ; Length of string
jz GD1 ; If 0, exit
mov al,'\' ; Not root, append \
stosb
GD1: mov ax,di
mov dx,es
pop ds
ret 4
GetDirectory ENDP
; FUNCTION InitExecSwap(LastToSave :Pointer; SwapFileName :String) :Boolean;
;
; 10d LastToSave (4)
; 06d ^SwapFileName (4)
; 02d RetAddr (4)
; BP -> BP
; 04d ^Name (4) ; Name part of path
; 08d Value (4) ; Timer value
NamePart equ (dword ptr [bp-4])
TimerValue equ (dword ptr [bp-8])
InitExecSwap PROC FAR
push bp
mov bp,sp ; Stack frame
sub sp,8 ; Local variables
mov al,EmsAllocatedF ; EMS or File allocated?
or al,FileAllocatedF
jz IE1 ; no, continue
xor al,al ; yes, exit (False)
jmp IEDone
; Work out bytes to swap
IE1: push [bp+12] ; Seg(LastToSave^)
push [bp+10] ; Ofs(LastToSave^)
call Normalize
mov [bp+12],dx
mov [bp+10],ax ; LastToSave := Normalize(LastToSave)
push cs ; Seg(FirstToSave)
mov ax,OFFSET FirstToSave ; Ofs(FirstToSave)
push ax
call Normalize ; DX:AX = Normalize(FirstToSave)
xchg [bp+12],dx
xchg [bp+10],ax ; LastToSave <=> DX:AX
sub ax,[bp+10]
sbb dx,[bp+12] ; DX:AX - LastToSave
mov BytesSwappedCS.lo, ax
mov BytesSwappedCS.hi, dx ; BytesSwappedCS = DX:AX
or dx,dx
js IE20 ; Jump if Negative
or ax,dx
jnz IE2 ; Jump if not zero
IE20: xor al,al ; Non-Positive amount, exit (False)
jmp IEDone
; Check if EMS installed
IE2: call EmsInstalled
or al,al ; Installed?
jz IE3 ; No, do disk
les ax,[BytesSwappedCS]
mov dx,es
add ax,EmsPageSize-1
adc dx,0 ; DX:AX = BytesSwappedCS+EmsPageSize-1
mov bx,EmsPageSize
div bx ; AX = DX:AX / EmsPageSize
push ax ; AX = pages to allocate
call AllocateEmsPages
mov EmsHandle,ax ; EmsHandle := AllocateEmsPages;
cmp ax,0FFFFh ; error?
je IE3 ; yes, do disk
mov EmsAllocatedF, 1 ; EmsAllocatedF := True;
call EmsPageFrame
mov FrameSeg,ax ; FrameSeg := EmsPageFrame;
or ax,ax
jz IE3 ; if 0, do disk
mov al,1
jmp IEDone ; Exit (True)
; Do Disk swapping
; Get a swap file name
IE3: push ds ; Save DS
lds si,[bp+6] ; DS:SI -> SwapFileName
MovSeg es,cs
mov di,OFFSET SwapName ; ES:DI -> SwapName
cld
lodsb ; Get length
or al,al
jz IE34 ; No path specified
cmp al,79-14 ; Truncate if path too long
jb IE30
mov al,79-14
IE30: cbw
mov cx,ax
rep movsb ; Now ES:DI -> char past name
jmp short IE33
IE34: call DefaultDrive ; Get current directory
stosb ; Store drive letter
mov al,':'
stosb
mov al,'\'
stosb ; D:\
push es
push di
call GetDirectory
mov es,dx
mov di,ax ; ES:DI = GetDirectory(ES:DI)
IE33: mov NamePart.lo,di
mov NamePart.hi,es ; Save pointer to name
xor ax,ax
mov ds,ax
mov ax,ds:[046Ch] ; Get timer counter
mov TimerValue.lo,ax
mov ax,ds:[046Eh]
mov TimerValue.hi,ax ; TimerValue := TimerCounter
IE32: push NamePart.hi
push NamePart.lo
push TimerValue.hi
call HexPrint ; DX:AX=HexPrint(NamePart, HiWord(TimerValue))
push dx
push ax
push TimerValue.lo
call HexPrint ; DX:AX=HexPrint(DX:AX, LoWord(TimerValue))
mov es,dx
mov di,ax
mov al,'.'
stosb
mov al,'$'
stosb
stosb
stosb
xor al,al
stosb ; _strcpy(DX:AX, ".$$$\0");
push cs
mov ax,OFFSET SwapName
push ax
call CanOpen
or al,al
jz IE31 ; IF Not CanOpen(SwapName) goto ok
add TimerValue.lo,1
adc TimerValue.hi,0 ; Inc(TimerValue)
jmp IE32 ; loop
IE31: pop ds ; Restore DS
MovSeg es,cs
mov di,OFFSET SwapName ; ES:DI -> SwapName
cmp byte ptr es:[di+1],':' ; Drive specified?
jne IE6 ; no drive specified
mov al,es:[di] ; Get drive letter
and al,not 32 ; Make upper case
jmp short IE7
IE6: call DefaultDrive ; AL = DefaultDrive
; Now AL = Drive letter and SwapName is ASCIIZ swap file name
IE7: sub al,40h ; convert to number
push ax
call DiskFree ; DX:AX = DiskFree(al)
sub ax,BytesSwappedCS.lo
sbb dx,BytesSwappedCS.hi ; DX:AX - BytesSwappedCS
jbe IE8 ; too little space, jump
call AllocateSwapFile
or al,al
jz IE9 ; AL=0, failed
mov al,1 ; AL=1, ok
jmp short IE9
IE8: xor al,al
IE9: mov FileAllocatedF,al
IEDone: mov sp,bp
pop bp ; AL = Result
ret 8
InitExecSwap ENDP
; FUNCTION BytesSwapped :LongInt;
BytesSwapped PROC FAR
les ax,BytesSwappedCS
mov dx,es
ret
BytesSwapped ENDP
; FUNCTION EmsAllocated :Boolean;
EmsAllocated PROC FAR
mov al,EmsAllocatedF
ret
EmsAllocated ENDP
; FUNCTION FileAllocated :Boolean;
FileAllocated PROC FAR
mov al,FileAllocatedF
ret
FileAllocated ENDP
Code ENDS
END